GroundwaterRiverUpdate Subroutine

public subroutine GroundwaterRiverUpdate(waterDepth, topWidth)

Update river-groundwater exchange fluxes

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: waterDepth

river water depth (m)

type(grid_real), intent(in) :: topWidth

river top width (m)


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: area
integer(kind=short), public :: i
integer(kind=short), public :: j
real(kind=float), public :: riverWSE
real(kind=float), public :: waterTable

Source Code

SUBROUTINE GroundwaterRiverUpdate &
!
( waterDepth, topWidth )

IMPLICIT NONE

!Arguments with intent (in):
TYPE (grid_real), INTENT(IN) :: waterDepth !!river water depth (m)
TYPE (grid_real), INTENT(IN) :: topWidth !!river top width (m)


!local variables:
INTEGER (KIND = short) :: i, j
REAL (KIND = float) :: riverWSE !river water surface elevation (m asl)
!TYPE (grid_real) :: waterTable  !!aquifer water table (m)
REAL (KIND = float) :: waterTable
REAL (KIND = float) :: area

!-----------------------------end of declarations------------------------------

volumeRiverToGroundwater = 0.
volumeGroundwaterToRiver = 0.

!waterTable = basin % aquifer (1) % head1

DO i = 1, riverGroundwaterID % idim
    DO j = 1, riverGroundwaterID % jdim
        IF ( riverGroundwaterID % mat (i,j) /= &
             riverGroundwaterID % nodata ) THEN 
            waterTable = basin % aquifer (1) % head1 % mat (i,j)
            riverWSE = waterDepth % mat (i,j) + riverDem % mat (i,j)
            area = CellArea (riverGroundwaterID, i, j)
            
            IF ( waterTable > riverWSE ) THEN
                
                groundwaterToRiver % mat (i,j) = &
                   ( waterTable - riverWSE )              * & !head difference
                     streambedConductivity % mat (i,j)    / & !conductivity
                     streambedThickness % mat (i,j)       * & !thickness
                     topWidth % mat (i,j)                 * & !river width
                     area ** 0.5                             !cell size
                
                riverToGroundwater % mat (i,j) = 0.
                
            ELSE  IF ( waterTable  <  riverWSE .AND. &
	                   waterTable  >  riverDem % mat (i,j) ) THEN
                
               ! when waterdepth > 10 cm, compute river discharge toward groundwater  
	           IF ( waterDepth % mat (i,j) > 0.10 ) THEN   
                   riverToGroundwater % mat(i,j) =             &
                       ( riverWSE - waterTable )             * & !head difference
                         streambedConductivity % mat (i,j)   / & !conductivity
                         streambedThickness % mat (i,j)      * & !thickness
                         topWidth % mat (i,j)                * & !river width
                         area ** 0.5                             !cell size
                   
                   groundwaterToRiver % mat (i,j) = 0.
			   ELSE
			       riverToGroundwater % mat(i,j) = 0.
               END IF
               
          ELSE  IF ( waterTable < riverDem % mat (i,j) ) THEN 
	            ! when waterdepth > 10 cm, compute river discharge toward groundwater   
	           IF (  waterDepth % mat (i,j) > 0.10 ) THEN  
	                riverToGroundwater % mat(i,j) =            &      
                         waterDepth % mat (i,j)              * & !head
                         streambedConductivity % mat (i,j)   / & !conductivity
                         streambedThickness % mat (i,j)      * & !thickness
                         topWidth % mat (i,j)                * & !river width
                         area ** 0.5      !cell size
                    
                    groundwaterToRiver % mat (i,j) = 0.
        
			   ELSE
			       riverToGroundwater % mat(i,j) = 0.
               END IF
                
            
          END IF
            
          volumeRiverToGroundwater = volumeRiverToGroundwater + &
                                     riverToGroundwater % mat (i,j) * &
                                     dtGroundwater
          volumeGroundwaterToRiver = volumeGroundwaterToRiver + &
                                     groundwaterToRiver % mat (i,j) * &
                                     dtGroundwater
            
            
        END IF
    END DO
END DO


RETURN
END SUBROUTINE GroundwaterRiverUpdate